CronSchedule.f90 Source File

Module to manage process scheduling



Source Code

!! Module to manage process scheduling
!|author:  <a href="mailto:giovanni.ravazzani@polimi.it">Giovanni Ravazzani</a>
! license: <a href="http://www.gnu.org/licenses/">GPL</a>
!    
!### History
!
! current version 1.0 - 28th March 2024  
!
! | version  |  date       |     comment   |
! |----------|-------------|---------------|
! | 1.0      | 28/Mar/2024 | Original code |
! | 1.1      | 03/Apr/2024 | function CronNextTime |
!   
!
!### License  
! license: GNU GPL <http://www.gnu.org/licenses/>
!
! This file is part of 
!
!   MOSAICO -- MOdular library for raSter bAsed hydrologIcal appliCatiOn.
! 
!   Copyright (C) 2011 Giovanni Ravazzani
!
!### Code Description 
!   Language:           Fortran 90. 
!
!   Software Standards: "European Standards for Writing and  
!   Documenting Exchangeable Fortran 90 Code". 
! 
!### Module Description: 
!   Set of fortran routines to manage process scheduling.
!   The module mimics the way CRONTAB is used on Linux
!   operating system to schedule processes.
!   Firstly a string is parsed to set when a process is started. 
!   The function `CronParseString` is called to parse the string.
!   The string is an expression made of five fields which represent 
!   the time to start a process: 
!
!```    
! |------------- minute (0-59)
! | |------------- hour (0-23)
! | | |------------ day of the month (1-31)
! | | | |------------ month (1-12)
! | | | | |------------ day of the week (0-6) (Sunday to Saturday)
! | | | | |
! | | | | |
! | | | | |
! * * * * * 
!```    
! Some examples:
!
!  `0 * * * *`  once an hour at the beginning of the hour
!
!  `0 0 * * *`  once a day at midnight
!
!  `0 0 * * 0`  once a week at midnight on Sunday
!
!  `0 0 1 * *`  once a month at midnight of the first day of the month
!
!  `0 0 1 1 *`  once a year at midnight of 1 January
!
! The function `CronIsTime` check when the time to execute a process is reached.
!
! References:
!
!   https://en.wikipedia.org/wiki/Cron
! 
!
MODULE CronSchedule

! 
! Modules used: 
! 
         
USE DataTypeSizes ,ONLY: & 
    ! Imported Parameters:  
    short,&
    float

USE StringManipulation, ONLY: &
    !Imported routines:
    StringCompact, &
    StringTokenize, &
    StringToLong

USE Chronos, ONLY : &
    !Imported types:
    DateTime, &
    !Imported routines:
    GetMinute, &
    GetHour, &
    GetDay, &
    GetMonth, &
    GetDayOfWeek, &
    !Imported operands:
    ASSIGNMENT( = ), &
    OPERATOR (+)

IMPLICIT NONE 


! Global (i.e. public) Declarations: 
! Global Procedures:
PUBLIC :: CronParseString
PUBLIC :: CronIsTime
PUBLIC :: CronNextTime


! Global Type Definitions: 
TYPE:: CronTab
	INTEGER (KIND = short) :: minutes (0:59)
    INTEGER (KIND = short) :: hours (0:23)
    INTEGER (KIND = short) :: daysOfMonth (31)
    INTEGER (KIND = short) :: months (12)
    INTEGER (KIND = short) :: daysOfWeek (0:6)
    CHARACTER (LEN = 300)  :: string
END TYPE CronTab


!=======         
CONTAINS
!======= 
! Define procedures contained in this module. 

!==============================================================================
!| Description:
!  parse cron string
!  
SUBROUTINE CronParseString &
!
(cronString, cron)

IMPLICIT NONE

!Arguments with intent (in):
CHARACTER (LEN = *), INTENT (IN) :: cronString

!Arguments with intent (out):
TYPE ( CronTab ), INTENT (OUT) :: cron 

!local declarations:
CHARACTER (LEN = 100) :: string
CHARACTER (len=100), POINTER :: targs (:), args (:)
INTEGER (KIND = short) :: tnargs, nargs, i, j, k
INTEGER (KIND = short) :: minute, hour, dayOfMonth, month, dayOfWeek

!-------------------------end of declarations----------------------------------

!clean time string
string =  StringCompact ( cronString )

!save cron string
cron % string = string

!split string
CALL StringTokenize (string = string, delims = ' ', &
                     args = targs, nargs = tnargs)

!search for minutes
cron % minutes = 0
IF ( targs (1) (1:1) == '*' ) THEN
    cron % minutes = 1
ELSE IF ( INDEX (targs (1), ',' )  > 0   ) THEN
    CALL StringTokenize (string = targs (1), delims = ',', &
                         args = args, nargs = nargs)
    DO i = 1, nargs
        minute = StringToLong (args (i) )
        cron % minutes ( minute ) = 1
    END DO
ELSE IF ( INDEX (targs (1), '-' )  > 0   ) THEN
    CALL StringTokenize (string = targs (1), delims = '-', &
                         args = args, nargs = nargs)
    j = StringToLong (args (1) )
    k = StringToLong (args (2) )
    DO i = j, k
        cron % minutes ( i ) = 1
    END DO
ELSE 
    minute = StringToLong ( targs (1) )
    cron % minutes ( minute ) = 1
END IF



!search for hours
cron % hours = 0
IF ( targs (2) (1:1) == '*' ) THEN
    cron % hours = 1
ELSE IF ( INDEX (targs (2), ',' )  > 0   ) THEN
    CALL StringTokenize (string = targs (2), delims = ',', &
                         args = args, nargs = nargs)
    DO i = 1, nargs
        hour = StringToLong (args (i) )
        cron % hours ( hour ) = 1
    END DO
ELSE IF ( INDEX (targs (2), '-' )  > 0   ) THEN
    CALL StringTokenize (string = targs (2), delims = '-', &
                         args = args, nargs = nargs)
    j = StringToLong (args (1) )
    k = StringToLong (args (2) )
    DO i = j, k
        cron % hours ( i ) = 1
    END DO
ELSE 
    hour = StringToLong ( targs (2) )
    cron % hours ( hour ) = 1
END IF


!search for days of month
 cron % daysOfMonth = 0
IF ( targs (3) (1:1) == '*' ) THEN
    cron % daysOfMonth = 1
ELSE IF ( INDEX (targs (3), ',' )  > 0   ) THEN
    CALL StringTokenize (string = targs (3), delims = ',', &
                         args = args, nargs = nargs)
    DO i = 1, nargs
        dayOfMonth = StringToLong (args (i) )
        cron % daysOfMonth ( dayOfMonth ) = 1
    END DO
ELSE IF ( INDEX (targs (2), '-' )  > 0   ) THEN
    CALL StringTokenize (string = targs (3), delims = '-', &
                         args = args, nargs = nargs)
    j = StringToLong (args (1) )
    k = StringToLong (args (2) )
    DO i = j, k
        cron % daysOfMonth ( i ) = 1
    END DO
ELSE 
    dayOfMonth = StringToLong ( targs (3) )
    cron % daysOfMonth ( dayOfMonth ) = 1
END IF


!search for months
cron % months = 0
IF ( targs (4) (1:1) == '*' ) THEN
    cron % months = 1
ELSE IF ( INDEX (targs (4), ',' )  > 0   ) THEN
    CALL StringTokenize (string = targs (4), delims = ',', &
                         args = args, nargs = nargs)
    DO i = 1, nargs
        month = StringToLong (args (i) )
        cron % months ( month ) = 1
    END DO
ELSE IF ( INDEX (targs (2), '-' )  > 0   ) THEN
    CALL StringTokenize (string = targs (4), delims = '-', &
                         args = args, nargs = nargs)
    j = StringToLong (args (1) )
    k = StringToLong (args (2) )
    DO i = j, k
        cron % months ( i ) = 1
    END DO
ELSE 
    month = StringToLong ( targs (4) )
    cron % months ( month ) = 1
END IF


!search for days of week
cron % daysOfWeek = 0
IF ( targs (5) (1:1) == '*' ) THEN
    cron % daysOfWeek = 1
ELSE IF ( INDEX (targs (5), ',' )  > 0   ) THEN
    CALL StringTokenize (string = targs (5), delims = ',', &
                         args = args, nargs = nargs)
    DO i = 1, nargs
        dayOfWeek = StringToLong (args (i) )
        cron % daysOfWeek ( dayOfWeek ) = 1
    END DO
ELSE IF ( INDEX (targs (2), '-' )  > 0   ) THEN
    CALL StringTokenize (string = targs (5), delims = '-', &
                         args = args, nargs = nargs)
    j = StringToLong (args (1) )
    k = StringToLong (args (2) )
    DO i = j, k
        cron % daysOfWeek ( i ) = 1
    END DO
ELSE 
    dayOfWeek = StringToLong ( targs (5) )
    cron % daysOfWeek ( dayOfWeek ) = 1
END IF

RETURN

END SUBROUTINE CronParseString


!==============================================================================
!| Description:
!  returns true if it is time to start a process
!  
FUNCTION CronIsTime &
!
(time, cron)  &
!
RESULT (yes)

IMPLICIT NONE

!Arguments with intent (in):
TYPE (DateTime), INTENT (IN) :: time
TYPE (CronTab),  INTENT (IN) :: cron 

!local declarations:
LOGICAL :: yes
!-------------------------------------end of declarations----------------------


yes = .FALSE.

IF ( cron % minutes     ( GetMinute    (time) ) == 1 .AND. &
     cron % hours       ( GetHour      (time) ) == 1 .AND. & 
     cron % daysOfMonth ( GetDay       (time) ) == 1 .AND. &
     cron % months      ( GetMonth     (time) ) == 1 .AND. &
     cron % daysOfWeek  ( GetDayOfWeek (time) ) == 1 ) THEN
    yes = .TRUE.
END IF


RETURN
END FUNCTION CronIsTime

!==============================================================================
!| Description:
!  returns the next time to start a process given the current time
!  
FUNCTION CronNextTime &
!
(time, cron)  &
!
RESULT (next)

IMPLICIT NONE

!Arguments with intent (in):
TYPE (DateTime), INTENT (IN) :: time  !!current time
TYPE (CronTab),  INTENT (IN) :: cron  !!cron table

!local declarationsnext
TYPE (DateTime) :: next
LOGICAL :: isTime
INTEGER (KIND = short) :: dt = 60 !! second

!-------------------------------------end of declarations----------------------

isTime = .FALSE.
next = time + dt
DO WHILE ( .NOT. isTime )
    isTime = CronIsTime (next, cron)
    next = next + dt
END DO

RETURN
END FUNCTION CronNextTime

END MODULE CronSchedule